perm filename CODE.OLD[IP,NET] blob
sn#712322 filedate 1983-05-25 generic text, type C, neo UTF8
COMMENT ⊗ VALID 00008 PAGES
C REC PAGE DESCRIPTION
C00001 00001
C00003 00002 INEMPT INPT INPTM INPT2 INPT2A INPT3 INPT4 INPT5 INPT6 INPT7 INPCLS INPCL1
C00011 00003 ROUTINES TO PROVIDE THE PROPER 'WILL', 'WONT', 'DO', 'DONT' RESPONSES. WILL WONT DO DONT TLNRSP TLNOCH TLNOCH TLNOC1 IGNXPF IGNXPT CLRXPT
C00017 00004 repeat 0,< this is now done at IMPSET
C00020 00005 CONECT: XCTR XR,[MOVE AC2,HLOC(UUO)] Get host number from user
C00022 00006 Here to turn on the scanner if it is off. Better not have been turned off
C00024 00007 Here when there are not enough buffers to send an output message.
C00025 00008 Code for debugging lost buffers
C00028 ENDMK
C⊗;
;INEMPT INPT INPTM INPT2 INPT2A INPT3 INPT4 INPT5 INPT6 INPT7 INPCLS INPCL1
;Subroutine to check for data in current input stream. Call with scanner off
;and TOPS-10 ACs set up. Non-skip return if there's data, skip return if empty.
;This code based on INBYTC in IMPSER.MAC.
INEMPT: SKIPLE IBFBC(F) ;Any bytes in current buffer?
JRST CPOPJ1 ;Yes.
PUSHJ P,INBUFR↑ ;Set up input buffer (in IMPSER.MAC)
POPJ P, ;Out of buffers. Take error return
MOVEM T2,IBFBC(F) ;Set byte count
HRLI T1,(POINT 8) ;Make byte pointer
MOVEM T1,IBFPNT(F) ;Save pointer
JRST INEMPT ;See if it's empty
;Common input routine. Enter with user address in TAC1 and desired word count
;in TAC. Returns count of words transferred in RH(DAT) and byte ptr to last byte
;transferred in LH(DAT). Returns +1 if error or no data available, +2 on some
;data transferred.
INPT: PUSHJ P,UUOIOK ; MAKE SURE HOST ALIVE AND ALL
POPJ P, ; HOST DEAD
INPTM: SETZ DAT, ; CLEAR WORD COUNT
;Read data out of input list and into user core. Some of this code similar to
;INPT in IMPSER.MAC, though cleaned up a bit. Main difference is that we BLT
;data from input stream into user core instead of moving it byte-by-byte.
PUSHACS ;Get into TOPS-10 mode
SETT10
SETAC(P1,TAC1) ;User address to store data
SETAC(P2,TAC) ;Desired word count
SETAC(P3,DAT) ;Words transferred
MOVSI S,ALLWAT!IOBRKF!IO!IOFST
ANDCAM S,IMPIOS(F)
HRRI S,IODATA
ANDCAB S,DEVIOS(F) ;CLEAR FLAGS
TLNN S,IOBEG ;FIRST TIME AROUND?
JRST INPT2 ;NO
SETZM ISHREG(F) ;YES
MOVSI S,IOFST!IOBEG ;FIRST IO FLAG
XORB S,DEVIOS(F)
INPT2: MOVSI S,IDATWT
IORM S,IMPIOS(F)
IORB S,DEVIOS(F) ;SET IO WAIT FLAGS
OFFSCN ; avoid anarchy
PUSHJ P,INEMPT ;CALL CHECK ROUTINE
JRST INPT3 ;DATA!
PUSHJ P,TCPICK↑ ;OPEN? (in TCPSER.MAC)
JRST [ ONSCN ;NO
JRST INPCLS] ;Return error to caller with WAITS ACs
SKIPE OKFLAG
SKIPE STOPFLG ;IMP OK?
JRST INPT2A ;NO
PUSHJ P,IMPW60 ;WAIT
JRST INPT2 ;TRY FROM TOP
;Here if IMP not OK.
INPT2A: ONSCN
POPACS ;Back to WAITS mode
JRST IMPLUZ
;Here we move data from the input stream into user core.
INPT3: ONSCN
HLRZ T1,IBFPNT(F)
CAIN T1,(POINT 8) ;Are we on a word boundary?
JRST INPT4 ;Yes
CAIE T1,(POINT 8,0,31) ;It may look like this instead
PUSHJ P,IMPBUG ;Nope -- totally confused
AOS T1,IBFPNT(F) ;If so, we fix it up
HRLI T1,(POINT 8)
MOVEM T1,IBFPNT(F)
INPT4: MOVE T2,IBFBC(F) ;Number of bytes in this buffer
;JJW - we may have to be more careful here.
ADDI T2,<1⊗WD2BYT>-1 ;Round up to multiple of a word
LSH T2,BYT2WD ;Convert to words
CAILE T2,(P2) ;DOES THE USER WANT LESS THAN THERE IS?
MOVEI T2,(P2) ;YES, JUST GIVE HIM WHAT HE WANTS
MOVEI T3,(P1) ;COPY OF USER'S ADDRESS
MOVE T1,IBFPNT(F)
HRLI T3,(T1) ;SOURCE,,RELATIVE DEST.
MOVEI T4,(P1) ;FIRST DESTINATION
ADDI T4,-1(T2) ;PLUS WC-1=LAST DEST.
XCTR XBLTW,[BLT T3,(T4)] ;MOVE DATA FROM FREE STG TO USER.
ADDM T2,IBFPNT(F) ;Update pointer into input stream
ADDI P3,(T2) ;ADD INTO NUMBER OF WORDS TRANSFERRED
SUBI P2,(T2) ;NOTE THAT HE HAS GOTTEN THAT MANY WORDS
ADDI P1,(T2) ;INCREMENT USER ADDRESS
SAVAC(TAC1,P1) ;Store these guys now
SAVAC(TAC,P2) ;Store these guys now
SAVAC(DAT,P3)
MOVEI T3,(T2) ;Adjust byte count for current buffer
LSH T3,WD2BYT
SUBM T3,IBFBC(F)
MOVNS IBFBC(F)
ADDM T2,IBFBYT(F) ;Also this counter
;Done with one buffer in input stream. Try for another maybe.
OFFSCN ;Be careful again
JUMPG P2,INPT5 ;Jump if he wants more
PUSHJ P,INEMPT ;Doesn't. See if any more in stream
SKIPA
JRST INPT6 ;Empty
MOVEI S,IODATA ;Set data flag
IORB S,DEVIOS(F)
JRST INPT7
INPT5: PUSHJ P,INEMPT ;Is there any more in input stream?
JRST INPT3 ;Yes, go process it.
;Input stream exhausted before user buffer.
MOVEI S,IODATA ;Clear input data flag
ANDCAB S,DEVIOS(F)
;Input stream exhausted
INPT6: PUSHJ P,TCPIFN↑ ;Test for closed (in TCPSER.MAC)
JRST [ ;Closed. Scanner now on. Tell user about EOF
PUSHJ P,INPCLS ;Sets up WAITS ACs
JRST CPOPJ1]
;Here when done.
INPT7: PUSHJ P,TCPWUP↑ ;Update window information (in TCPSER.MAC)
ONSCN ;Allow interrupts again
PUSHJ P,IMPWK1↑ ;Clear flags and such (in IMPSER.MAC)
JRST POPPJ1 ;Indicate success
;Here if socket not open (with scanner back on). Returns with WAITS ACs set up.
INPCLS: MOVSI S,IOEND ;End of file
IORB S,DEVIOS(F)
SKIPN IBFTHS(F) ;Any data in buffers?
TLNN S,IOFST ;No was any input?
JRST INPCL1
MOVEI S,IOIPM ;No. Error
IORB S,DEVIOS(F)
INPCL1: PUSHJ P,IMPWK1↑
JRST POPPOJ
;ROUTINES TO PROVIDE THE PROPER 'WILL', 'WONT', 'DO', 'DONT' RESPONSES. ;⊗ WILL WONT DO DONT TLNRSP TLNOCH TLNOCH TLNOC1 IGNXPF IGNXPT CLRXPT
WILL: JSP T1,TLNRSP ;'WILL'
WONT: JSP T1,TLNRSP ;'WONT'
DO: JSP T1,TLNRSP ;'DO'
DONT: JSP T1,TLNRSP ;'DONT'
TLNRSP: SUBI T1,WILL+1-.TNWIL ;BUILD THE RESPONSE COMMAND CHARACTER
HRLM T1,(P) ;SAVE IT
PUSHJ P,CLRXPT ;CLEAR OUT THE RIGHT REPLY EXPECTED BIT
POPJ P, ;WAS ON...IGNORE
MOVEI T3,.TNIAC ;SEND 'IAC'
IFWAITS<SCNOFF> ;No interference between these characters
PUSHJ P,TLNOCH
NOWAITS<
SETZ T3, ;SEND A NULL (IAC NULL TERMINATES PROCESSING, SO NEG MAKE IT OUT)
PUSHJ P,TLNOCH
>;NOWAITS
HLRZ T3,(P) ;SEND COMMAND
PUSHJ P,TLNOCH
LDB T3,PTLNop ;SEND OPTION NAME
IFWAITS< ;TOPS-10 code just falls into TLNOCH here
PUSHJ P,TLNOCH
SCNON
PJRST XMTQIT ;Make these chars go out right away
>;IFWAITS
NOWAITS<
TLNOCH: IORI T3,400 ;SET IMAGE BIT TO DISABLE FURTHER MANGLING
SKIPGE TTYLIN(F) ;HOW IS TTY CONNECTED?
PJRST CCTYO9## ;SERVER TELNET, SEND IT
PUSH P,F ;USER TELNET, FAKE USER TTY INPUT
PUSHJ P,RECIMP##
;(271) JFCL ;INPUT BUFFER FULL (SHOULDN'T HAPPEN)
JRST FPOPJ## ;RESTORE IMP DDB POINTER
>;NOWAITS
IFWAITS<
;Scanner must be OFF when calling TLNOCH
TLNOCH::IORI T3,400 ;SET IMAGE BIT TO DISABLE FURTHER MANGLING
SKIPGE TTYLIN(F) ;HOW IS TTY CONNECTED?
JRST TLNOC1 ;SERVER TELNET, SEND IT
PUSHJ P,IMPBUG## ;User Telnet can't happen
POPJ P,
TLNOC1: PUSH P,DDB ;Save IMP DDB
MOVE DDB,TTYTAB##(U) ;Get the TTY DDB for this line
IFN T3-TEM,<PUSH P,TEM ;Get character in right WAITS AC
MOVE TEM,T3>
PUSHJ P,PUTCRS## ;Stuff it into the output buffer (in TTYSER)
SKIPN TEM ;See if we overflowed
PUSHJ P,IMPBUG## ;Yes. Bad lossage
IFN T3-TEM,<POP P,TEM>
POP P,DDB ;Restore IMP DDB
POPJ P,
>;IFWAITS
repeat 0,< ;this is now done at IMPSET
;First see if there's an existing DDB we can connect to.
XCTR XR,[SKIPN T3,LSLOC(M)] ;Get requested local port
JRST LISTN4 ;Can't match to an existing connection
PUSH P,F ;Push the DDB we've got
MOVEI F,IMPDDB ;Point at prototype
OFFSCN ;No interference, please
LISTN2: HLRZ F,DEVSER(F) ;Advance to next IMP DDB
CAIN F,IMP.NX ;Last one?
JRST LISTN3
SKIPLE T1,STATE(F) ;Is it closed?
SKIPE TTYLIN(F) ;Or in use for a Telnet connection?
JRST LISTN2 ;Yes, skip it
LDB J,PJOBN ;Does it have an owner?
JUMPN J,LISTN2 ;Yes, skip it
CAME T3,LCLPRT(F) ;Is it the port we want?
JRST LISTN2 ;No
;Here we've found a legal DDB to give this job. Flush his old one.
ONSCN ;Interrupts safe again
EXCH F,(P) ;Get back the old DDB
TCPCAL(CLOS) ;Close any connection and flush DDB
POP P,F ;Now get the DDB for the new connection
MOVE T4,UCHN-20(P) ;Get UCHN from UUO into T4
MOVEM F,USRJDA(T4) ;Store new DDB
SAVAC(DDB,F) ;And make sure it's popped back
CAIGE T1,S%ESTB↑ ;Are we already established?
XCTR XR,[SKIPN WFLOC(M)] ;Or doesn't he care?
POPJ P, ;Then return right now
PUSHJ P,ESTBWT↑ ;Wait till we get there (turns off scanner)
JFCL
JRST SCNONJ ;Interrupts on and return
LISTN3: ONSCN ;No useful DDB found
POP P,F ;Get back our DDB
;Here to listen for a connection
LISTN4:
>;repeat 0
CONECT: XCTR XR,[MOVE AC2,HLOC(UUO)] ;Get host number from user
TLNE AC2,740000 ;Left 4 bits 0?
JRST NONIP ;No. Can't be an IP address.
LDB AC3,[POINT 8,AC2,11] ;Network number in IP format
CAIN AC3,ARPADR ;ARPAnet?
JRST IPADR ;Yes. Wouldn't be legal in NCP format.
CAIE AC3,ARPADR⊗3 ;ARPAnet in NCP format?
JUMPN AC3,UUOERR ;No. If not 0, punt.
NONIP: LDB AC3,[POINT 8,AC2,8] ;Network number in NCP format
SKIPN AC3
MOVEI AC3,ARPADR ;Default to ARPAnet
CAIE AC3,ARPADR ;Check network for legality
JRST UUOERR ;Unknown network
TDNE AC2,[400600,,000400] ;LEGAL NUMBER?
JRST UUOERR ;BLAST THIS LOSER OUT OF THE WATER!
TDNE AC2,[000177,,777000] ;OLD OR NEW STYLE NUMBER?
JRST CONNEW
DPB AC2,[POINT 6,AC2,20] ;STORE IMP NUMBER IN NEW FORMAT
LSH AC2,-6 ;RIGHT-ALIGN HOST NUMBER
;Here to turn on the scanner if it is off. Better not have been turned off
;twice because we only turn in back on once (one decrementing of SCNCNT).
↑SCNFIX:SKIPGE SCNCNT ;skip if scanner off
POPJ P, ;already on, leave well enough alone
SKIPG SCNCNT ;skip if off more than once
JRST SCNONJ ;just off once, turn it back on
PUSHJ P,BUGTRP ;was turned off twice at least!!
SETZM SCNCNT ;well fix it then?!
;fall into SCNONJ
;TOPS-10 code JSRs here to turn PIs back on. Address from previous JSR to
;PIOFFS is cleared so that we can tell whether the problem is in TOPS-10 code
;or WAITS code.
;FAIL code does NOT JSR here.
PIONS↑: 0
SETZM PIOFFS
MOVE 7,PIONS ;Get return address in a never-used AC (R) before CONO
CONO PI,PION
JRST (7)
;Here when there are not enough buffers to send an output message.
↑XOUTLZ:PUSH P,AC1 ;Save ACs used by DISMES
PUSH P,TEM
PUSHJ P,DISUSR
SIXBIT/NET/
PUSHJ P,DISMES
ASCIZ/Not enough buffers to send an IMP output message
/
POP P,TEM
POP P,AC1
PUSHJ P,DISFLUSH
PUSHJ P,DDTCALL
POPJ P,
Code for debugging lost buffers
Inserted just after IFN DEBUG <> in BUFGET in NETSUB:
IFWAITS<
BUFGT4: HRRZ T2,(P)
CAIE T2,GETME1+1 ;A loser?
CAIN T2,IMPMAK##+3
CAIA
JRST BUFGT5
PUSHJ P,PUSHIT## ;Save all ACs
SETZM CTYMAR##
PUSHJ P,DISMES##
ASCIZ/Allc /
MOVE TAC,T1-17(P)
PUSHJ P,DISLOC##
PUSHJ P,DISMES##
ASCIZ/ at /
MOVE TAC,P-17(P)
MOVE TAC,-1(TAC)
PUSHJ P,DISLOC##
PUSHJ P,DISCRLF##
PUSHJ P,POPIT##
BUFGT5:
>;IFWAITS
Inserted after BLT in BFCLR in NETSUB:
IFWAITS< ;Store trace info at end of buffer
MOVE T2,(P) ;Addr of creator
MOVEM T2,IMPBFS##-1(T1)
MOVE T2,-4(P) ;Addr of GETMES caller if (P) = GETME1
MOVEM T2,IMPBFS##-2(T1)
>;IFWAITS
Inserted at beginning of RELBUF in NETSUB:
IFWAITS<
JRST RELBF2 ;JFCL to print messages
PUSHJ P,PUSHIT## ;Save all ACs
SETZM CTYMAR##
PUSHJ P,DISMES##
ASCIZ/RELBUF called from /
MOVE TAC,P-17(P)
MOVE TAC,-1(TAC)
PUSHJ P,DISLOC##
PUSHJ P,DISCRLF##
PUSHJ P,POPIT##
RELBF2:
>;IFWAITS
Inserted after IDIVI in BUFREL in NETSUB:
IFWAITS<
PUSH P,T1
PUSH P,T2
IMULI T1,IMPBFS##
ADD T1,IMPBUF##
HLRZ T2,IMPBFS##-1(T1)
CAIE T2,GETME1+2
CAIN T2,IMPMAK##+4
CAIA
JRST [ POP P,T2
POP P,T1
JRST BUFRL2]
POP P,T2
PUSHJ P,PUSHIT## ;Save all ACs
SETZM CTYMAR##
PUSHJ P,DISMES##
ASCIZ/Rls /
MOVE TAC,T1-17(P)
PUSHJ P,DISLOC##
PUSHJ P,DISMES##
ASCIZ/ at /
MOVE TAC,P-17(P)
MOVE TAC,-1(TAC)
PUSHJ P,DISLOC##
PUSHJ P,DISCRLF##
PUSHJ P,POPIT##
POP P,T1
BUFRL2:
>;IFWAITS